hakyll/src/Hakyll/Core/CompiledItem.hs

47 lines
1.4 KiB
Haskell
Raw Normal View History

2010-12-28 10:12:45 +00:00
-- | A module containing a box datatype representing a compiled item. This
2011-02-11 12:30:55 +00:00
-- item can be of any type, given that a few restrictions hold:
--
-- * we need a 'Typeable' instance to perform type-safe casts;
--
-- * 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.
2010-12-28 10:12:45 +00:00
--
{-# LANGUAGE ExistentialQuantification #-}
module Hakyll.Core.CompiledItem
( CompiledItem (..)
2010-12-28 10:12:45 +00:00
, compiledItem
, unCompiledItem
) where
import Data.Binary (Binary)
2011-03-02 19:37:34 +00:00
import Data.Typeable (Typeable, cast, typeOf)
2011-01-14 07:50:34 +00:00
import Data.Maybe (fromMaybe)
2010-12-28 10:12:45 +00:00
import Hakyll.Core.Writable
-- | Box type for a compiled item
--
data CompiledItem = forall a. (Binary a, Typeable a, Writable a)
=> CompiledItem a
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 = CompiledItem
-- | Unbox a value from a 'CompiledItem'
--
unCompiledItem :: (Binary a, Typeable a, Writable a)
=> CompiledItem
-> a
2011-01-14 07:50:34 +00:00
unCompiledItem (CompiledItem x) = fromMaybe error' $ cast x
where
2011-03-02 19:37:34 +00:00
error' = error $ "Hakyll.Core.CompiledItem.unCompiledItem: "
++ "unsupported type (got " ++ show (typeOf x) ++ ")"