Micro-cleanup

This commit is contained in:
Jasper Van der Jeugt 2011-01-14 08:50:34 +01:00
parent 3ea3c52f53
commit 6e7dc0e58f
10 changed files with 19 additions and 20 deletions

View file

@ -11,6 +11,7 @@ module Hakyll.Core.CompiledItem
import Data.Binary (Binary)
import Data.Typeable (Typeable, cast)
import Data.Maybe (fromMaybe)
import Hakyll.Core.Writable
@ -34,6 +35,6 @@ compiledItem = CompiledItem
unCompiledItem :: (Binary a, Typeable a, Writable a)
=> CompiledItem
-> a
unCompiledItem (CompiledItem x) = case cast x of
Just x' -> x'
Nothing -> error "Hakyll.Core.CompiledItem.unCompiledItem: Unsupported type"
unCompiledItem (CompiledItem x) = fromMaybe error' $ cast x
where
error' = error "Hakyll.Core.CompiledItem.unCompiledItem: Unsupported type"

View file

@ -92,8 +92,7 @@ runCompilerJob compiler identifier provider route store modified =
runCompilerDependencies :: Compiler () a
-> ResourceProvider
-> Dependencies
runCompilerDependencies compiler provider =
runReader (compilerDependencies compiler) provider
runCompilerDependencies compiler = runReader (compilerDependencies compiler)
fromJob :: (a -> CompilerM b)
-> Compiler a b

View file

@ -65,12 +65,12 @@ reachableNodes set graph = reachable (setNeighbours set) set
sanitize' = S.filter (`S.notMember` visited)
neighbours' = setNeighbours (sanitize' next)
setNeighbours = S.unions . map (flip neighbours graph) . S.toList
setNeighbours = S.unions . map (`neighbours` graph) . S.toList
-- | Remove all dangling pointers, i.e. references to notes that do
-- not actually exist in the graph.
--
sanitize :: Ord a => DirectedGraph a -> DirectedGraph a
sanitize (DirectedGraph graph) = DirectedGraph $ M.map sanitize' $ graph
sanitize (DirectedGraph graph) = DirectedGraph $ M.map sanitize' graph
where
sanitize' (Node t n) = Node t $ S.filter (`M.member` graph) n

View file

@ -10,7 +10,7 @@ module Hakyll.Core.DirectedGraph.DependencySolver
import Prelude
import qualified Prelude as P
import Data.Set (Set)
import Data.Maybe (catMaybes)
import Data.Maybe (mapMaybe)
import qualified Data.Map as M
import qualified Data.Set as S
@ -48,7 +48,7 @@ order temp stack set graph@(DirectedGraph graph')
-- Check which dependencies are still in the graph
let tag = nodeTag node
deps = S.toList $ nodeNeighbours node
unsatisfied = catMaybes $ map (flip M.lookup graph') deps
unsatisfied = mapMaybe (`M.lookup` graph') deps
in case unsatisfied of
-- All dependencies for node are satisfied, we can return it and
@ -58,7 +58,7 @@ order temp stack set graph@(DirectedGraph graph')
-- There is at least one dependency left. We need to solve that
-- one first...
(dep : _) -> if (nodeTag dep) `S.member` set
(dep : _) -> if nodeTag dep `S.member` set
-- The dependency is already in our stack - cycle detected!
then cycleError
-- Continue with the dependency

View file

@ -17,7 +17,7 @@ import qualified Data.Set as S
--
data Node a = Node
{ nodeTag :: a -- ^ Tag identifying the node
, nodeNeighbours :: (Set a) -- ^ Edges starting at this node
, nodeNeighbours :: Set a -- ^ Edges starting at this node
} deriving (Show)
-- | Append two nodes. Useful for joining graphs.

View file

@ -17,7 +17,7 @@ import Hakyll.Core.Util.File
fileResourceProvider :: IO ResourceProvider
fileResourceProvider = do
list <- map parseIdentifier <$> getRecursiveContents "."
return $ ResourceProvider
return ResourceProvider
{ resourceList = list
, resourceString = readFile . toFilePath
, resourceLazyByteString = LB.readFile . toFilePath

View file

@ -59,7 +59,7 @@ idRoute = Route $ Just . toFilePath
-- > Just "posts/the-art-of-trolling.html"
--
setExtension :: String -> Route
setExtension exension = Route $ fmap (flip replaceExtension exension)
setExtension extension = Route $ fmap (`replaceExtension` extension)
. unRoute idRoute
-- | Modify a route: apply the route if the identifier matches the given

View file

@ -116,7 +116,7 @@ addCompilers :: (Binary a, Typeable a, Writable a)
-- ^ Compiler generating the other compilers
-> Rules
-- ^ Resulting rules
addCompilers identifier compiler = RulesM $ tell $ RuleSet mempty $
addCompilers identifier compiler = RulesM $ tell $ RuleSet mempty
[(identifier, compiler >>> arr makeRule )]
where
makeRule = MetaCompileRule . map (second box)

View file

@ -16,7 +16,6 @@ import Data.Monoid (mempty, mappend)
import Data.Typeable (Typeable)
import Data.Binary (Binary)
import System.FilePath ((</>))
import Control.Applicative ((<$>))
import Data.Set (Set)
import qualified Data.Set as S
@ -115,7 +114,7 @@ addNewCompilers oldCompilers newCompilers = Hakyll $ do
-- Find the old graph and append the new graph to it. This forms the
-- complete graph
completeGraph <- (mappend currentGraph) . hakyllGraph <$> get
completeGraph <- mappend currentGraph . hakyllGraph <$> get
liftIO $ writeDot "dependencies.dot" show completeGraph
@ -190,6 +189,6 @@ runCompilers ((id', compiler) : compilers) = Hakyll $ do
unHakyll $ runCompilers compilers
-- Metacompiler, slightly more complicated
MetaCompileRule newCompilers -> do
MetaCompileRule newCompilers ->
-- Actually I was just kidding, it's not hard at all
unHakyll $ addNewCompilers compilers newCompilers

View file

@ -89,7 +89,7 @@ pageRenderPandocWith :: P.ParserState
-> P.WriterOptions
-> Compiler (Page String) (Page String)
pageRenderPandocWith state options =
pageReadPandocWith state >>^ (fmap $ writePandocWith options)
pageReadPandocWith state >>^ fmap (writePandocWith options)
-- | The default reader options for pandoc parsing in hakyll
--