summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/CompiledItem.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll/Core/CompiledItem.hs')
-rw-r--r--src/Hakyll/Core/CompiledItem.hs40
1 files changed, 24 insertions, 16 deletions
diff --git a/src/Hakyll/Core/CompiledItem.hs b/src/Hakyll/Core/CompiledItem.hs
index e40ab56..85e85b3 100644
--- a/src/Hakyll/Core/CompiledItem.hs
+++ b/src/Hakyll/Core/CompiledItem.hs
@@ -1,3 +1,4 @@
+--------------------------------------------------------------------------------
-- | A module containing a box datatype representing a compiled item. This
-- item can be of any type, given that a few restrictions hold:
--
@@ -6,42 +7,49 @@
-- * we need a 'Binary' instance so we can serialize these items to the cache;
--
-- * we need a 'Writable' instance so the results can be saved.
---
-{-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE ExistentialQuantification #-}
module Hakyll.Core.CompiledItem
( CompiledItem (..)
, compiledItem
, unCompiledItem
) where
-import Data.Binary (Binary)
-import Data.Typeable (Typeable, cast, typeOf)
-import Data.Maybe (fromMaybe)
-import Hakyll.Core.Writable
+--------------------------------------------------------------------------------
+import Data.Binary (Binary)
+import Data.Maybe (fromMaybe)
+import Data.Typeable (Typeable, cast, typeOf)
+
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Writable
+
+--------------------------------------------------------------------------------
-- | Box type for a compiled item
--
data CompiledItem = forall a. (Binary a, Typeable a, Writable a)
=> CompiledItem a
deriving (Typeable)
+
+--------------------------------------------------------------------------------
instance Writable CompiledItem where
write p (CompiledItem x) = write p x
+
+--------------------------------------------------------------------------------
-- | Box a value into a 'CompiledItem'
---
-compiledItem :: (Binary a, Typeable a, Writable a)
- => a
- -> CompiledItem
+compiledItem :: (Binary a, Typeable a, Writable a) => a -> CompiledItem
compiledItem = CompiledItem
+
+--------------------------------------------------------------------------------
-- | Unbox a value from a 'CompiledItem'
---
-unCompiledItem :: (Binary a, Typeable a, Writable a)
- => CompiledItem
- -> a
+unCompiledItem :: (Binary a, Typeable a, Writable a) => CompiledItem -> a
unCompiledItem (CompiledItem x) = fromMaybe error' $ cast x
where
- error' = error $ "Hakyll.Core.CompiledItem.unCompiledItem: "
- ++ "unsupported type (got " ++ show (typeOf x) ++ ")"
+ error' = error $
+ "Hakyll.Core.CompiledItem.unCompiledItem: " ++
+ "unsupported type (got " ++ show (typeOf x) ++ ")"