summaryrefslogtreecommitdiff
path: root/src/Hakyll
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2013-03-09 17:54:08 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2013-03-09 17:54:08 +0100
commit5241e87f1692e488207b9a7ca2e5a592412f1583 (patch)
tree3f40fd30b6e208e4ee84b2a5c1fc8493a4e363b1 /src/Hakyll
parentdf1fb668881d7293405396fecaa45620bdf56ecc (diff)
downloadhakyll-5241e87f1692e488207b9a7ca2e5a592412f1583.tar.gz
Make http-conduit dependency optional
Diffstat (limited to 'src/Hakyll')
-rw-r--r--src/Hakyll/Check.hs37
1 files changed, 27 insertions, 10 deletions
diff --git a/src/Hakyll/Check.hs b/src/Hakyll/Check.hs
index a426f87..73606b3 100644
--- a/src/Hakyll/Check.hs
+++ b/src/Hakyll/Check.hs
@@ -1,4 +1,5 @@
--------------------------------------------------------------------------------
+{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Check
( Check (..)
@@ -8,22 +9,15 @@ module Hakyll.Check
--------------------------------------------------------------------------------
import Control.Applicative ((<$>))
-import Control.Exception (AsyncException (..),
- SomeException (..), handle, throw)
import Control.Monad (forM_)
import Control.Monad.Reader (ask)
import Control.Monad.RWS (RWST, runRWST)
-import Control.Monad.State (get, modify)
import Control.Monad.Trans (liftIO)
import Control.Monad.Writer (tell)
-import Data.List (intercalate, isPrefixOf)
+import Data.List (isPrefixOf)
import Data.Monoid (Monoid (..))
import Data.Set (Set)
import qualified Data.Set as S
-import Data.Typeable (cast)
-import GHC.Exts (fromString)
-import qualified Network.HTTP.Conduit as Http
-import qualified Network.HTTP.Types as Http
import System.Directory (doesDirectoryExist, doesFileExist)
import System.Exit (ExitCode (..))
import System.FilePath (takeDirectory, takeExtension, (</>))
@@ -31,13 +25,26 @@ import qualified Text.HTML.TagSoup as TS
--------------------------------------------------------------------------------
+#ifdef CHECK_EXTERNAL
+import Control.Exception (AsyncException (..),
+ SomeException (..), handle, throw)
+import Control.Monad.State (get, modify)
+import Data.List (intercalate)
+import Data.Typeable (cast)
import Data.Version (versionBranch)
+import GHC.Exts (fromString)
+import qualified Network.HTTP.Conduit as Http
+import qualified Network.HTTP.Types as Http
+import qualified Paths_hakyll as Paths_hakyll
+#endif
+
+
+--------------------------------------------------------------------------------
import Hakyll.Core.Configuration
import Hakyll.Core.Logger (Logger, Verbosity)
import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Util.File
import Hakyll.Web.Html
-import qualified Paths_hakyll as Paths_hakyll
--------------------------------------------------------------------------------
@@ -87,7 +94,12 @@ runChecker :: Checker a -> Configuration -> Verbosity -> Check
-> IO (a, CheckerWrite)
runChecker checker config verbosity check' = do
logger <- Logger.new verbosity
- let read' = CheckerRead config logger check'
+ let read' = CheckerRead
+ { checkerConfig = config
+ , checkerLogger = logger
+ , checkerCheck = check'
+ }
+
(x, _, write) <- runRWST checker read' S.empty
Logger.flush logger
return (x, write)
@@ -157,6 +169,7 @@ checkInternalUrl base url = case url' of
--------------------------------------------------------------------------------
checkExternalUrl :: String -> Checker ()
+#ifdef CHECK_EXTERNAL
checkExternalUrl url = do
logger <- checkerLogger <$> ask
needsCheck <- (== All) . checkerCheck <$> ask
@@ -190,6 +203,10 @@ checkExternalUrl url = do
failure logger (SomeException e) = case cast e of
Just UserInterrupt -> throw UserInterrupt
_ -> Logger.error logger (show e) >> return False
+#else
+checkExternalUrl _ = return ()
+#endif
+
--------------------------------------------------------------------------------