summaryrefslogtreecommitdiff
path: root/src/Hakyll
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll')
-rw-r--r--src/Hakyll/Core/CopyFile.hs29
-rw-r--r--src/Hakyll/Core/Writable.hs15
-rw-r--r--src/Hakyll/Web.hs6
3 files changed, 31 insertions, 19 deletions
diff --git a/src/Hakyll/Core/CopyFile.hs b/src/Hakyll/Core/CopyFile.hs
new file mode 100644
index 0000000..dbbaaa1
--- /dev/null
+++ b/src/Hakyll/Core/CopyFile.hs
@@ -0,0 +1,29 @@
+-- | Exports simple compilers to just copy files
+--
+{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-}
+module Hakyll.Core.CopyFile
+ ( CopyFile (..)
+ , copyFileCompiler
+ ) where
+
+import Control.Arrow ((>>^))
+import System.Directory (copyFile)
+
+import Data.Typeable (Typeable)
+import Data.Binary (Binary)
+
+import Hakyll.Core.ResourceProvider
+import Hakyll.Core.Writable
+import Hakyll.Core.Compiler
+import Hakyll.Core.Identifier
+
+-- | Newtype construct around 'FilePath' which will copy the file directly
+--
+newtype CopyFile = CopyFile {unCopyFile :: FilePath}
+ deriving (Show, Eq, Ord, Binary, Typeable)
+
+instance Writable CopyFile where
+ write dst (CopyFile src) = copyFile src dst
+
+copyFileCompiler :: Compiler Resource CopyFile
+copyFileCompiler = getIdentifier >>^ CopyFile . toFilePath
diff --git a/src/Hakyll/Core/Writable.hs b/src/Hakyll/Core/Writable.hs
index db53d9a..a3fd421 100644
--- a/src/Hakyll/Core/Writable.hs
+++ b/src/Hakyll/Core/Writable.hs
@@ -1,18 +1,13 @@
-- | Describes writable items; items that can be saved to the disk
--
-{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving,
- DeriveDataTypeable #-}
+{-# LANGUAGE FlexibleInstances #-}
module Hakyll.Core.Writable
( Writable (..)
- , CopyFile (..)
) where
-import System.Directory (copyFile)
import Data.Word (Word8)
import qualified Data.ByteString as SB
-import Data.Binary (Binary)
-import Data.Typeable (Typeable)
-- | Describes an item that can be saved to the disk
--
@@ -25,11 +20,3 @@ instance Writable [Char] where
instance Writable [Word8] where
write p = SB.writeFile p . SB.pack
-
--- | Newtype construct around 'FilePath' which will copy the file directly
---
-newtype CopyFile = CopyFile {unCopyFile :: FilePath}
- deriving (Show, Eq, Ord, Binary, Typeable)
-
-instance Writable CopyFile where
- write dst (CopyFile src) = copyFile src dst
diff --git a/src/Hakyll/Web.hs b/src/Hakyll/Web.hs
index ec05afb..482cf6d 100644
--- a/src/Hakyll/Web.hs
+++ b/src/Hakyll/Web.hs
@@ -1,8 +1,7 @@
-- | Module exporting commonly used web-related functions
--
module Hakyll.Web
- ( defaultCopyFile
- , defaultApplyTemplate
+ ( defaultApplyTemplate
) where
import Control.Arrow ((>>^))
@@ -14,9 +13,6 @@ import Hakyll.Core.ResourceProvider
import Hakyll.Web.Page
import Hakyll.Web.Template
-defaultCopyFile :: Compiler Resource CopyFile
-defaultCopyFile = getIdentifier >>^ CopyFile . toFilePath
-
defaultApplyTemplate :: Identifier -- ^ Template
-> Compiler (Page String) (Page String) -- ^ Compiler
defaultApplyTemplate identifier = require identifier (flip applyTemplate)