hakyll/src/Hakyll/Core/Identifier.hs

96 lines
3 KiB
Haskell
Raw Normal View History

2010-12-23 16:19:21 +00:00
-- | An identifier is a type used to uniquely identify a resource, target...
--
-- One can think of an identifier as something similar to a file path. An
-- identifier is a path as well, with the different elements in the path
-- separated by @/@ characters. Examples of identifiers are:
--
-- * @posts/foo.markdown@
--
-- * @index@
--
-- * @error/404@
--
2011-02-12 15:54:31 +00:00
-- The most important difference between an 'Identifier' and a file path is that
-- the identifier for an item is not necesserily the file path.
--
-- For example, we could have an @index@ identifier, generated by Hakyll. The
-- actual file path would be @index.html@, but we identify it using @index@.
--
-- @posts/foo.markdown@ could be an identifier of an item that is rendered to
-- @posts/foo.html@. In this case, the identifier is the name of the source
-- file of the page.
--
2011-03-20 16:17:39 +00:00
{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-}
2010-12-23 16:19:21 +00:00
module Hakyll.Core.Identifier
( Identifier (..)
2011-05-24 09:58:13 +00:00
, castIdentifier
2010-12-23 16:19:21 +00:00
, parseIdentifier
, toFilePath
2011-04-11 16:10:45 +00:00
, setGroup
2010-12-23 16:19:21 +00:00
) where
import Control.Arrow (second)
import Control.Applicative ((<$>), (<*>))
import Control.Monad (mplus)
import Data.Monoid (Monoid, mempty, mappend)
import Data.List (intercalate)
2010-12-23 16:19:21 +00:00
import Data.Binary (Binary, get, put)
2010-12-23 16:19:21 +00:00
import GHC.Exts (IsString, fromString)
2011-03-20 16:17:39 +00:00
import Data.Typeable (Typeable)
2010-12-23 16:19:21 +00:00
-- | An identifier used to uniquely identify a value
--
2011-05-24 09:58:13 +00:00
-- The @a@ is used to denote the type that the identifier points to. It is a
-- phantom type parameter, meaning you can safely change this if you know what
-- you are doing.
--
-- If the @a@ type is not known, Hakyll traditionally uses @Identifier ()@.
--
data Identifier a = Identifier
{ identifierGroup :: Maybe String
, identifierPath :: String
} deriving (Eq, Ord, Typeable)
2011-05-24 09:58:13 +00:00
instance Monoid (Identifier a) where
mempty = Identifier Nothing ""
Identifier g1 p1 `mappend` Identifier g2 p2 =
Identifier (g1 `mplus` g2) (p1 `mappend` p2)
2011-05-24 09:58:13 +00:00
instance Binary (Identifier a) where
put (Identifier g p) = put g >> put p
get = Identifier <$> get <*> get
2010-12-23 16:19:21 +00:00
2011-05-24 09:58:13 +00:00
instance Show (Identifier a) where
2011-04-12 07:00:36 +00:00
show i@(Identifier Nothing _) = toFilePath i
show i@(Identifier (Just g) _) = toFilePath i ++ " (" ++ g ++ ")"
2010-12-23 16:19:21 +00:00
2011-05-24 09:58:13 +00:00
instance IsString (Identifier a) where
2010-12-23 16:19:21 +00:00
fromString = parseIdentifier
2011-05-24 09:58:13 +00:00
-- | Discard the phantom type parameter of an identifier
--
castIdentifier :: Identifier a -> Identifier b
castIdentifier (Identifier g p) = Identifier g p
{-# INLINE castIdentifier #-}
2010-12-23 16:19:21 +00:00
-- | Parse an identifier from a string
--
2011-05-24 09:58:13 +00:00
parseIdentifier :: String -> Identifier a
parseIdentifier = Identifier Nothing
. intercalate "/" . filter (not . null) . split'
2010-12-23 16:19:21 +00:00
where
split' [] = [[]]
split' str = let (pre, post) = second (drop 1) $ break (== '/') str
in pre : split' post
-- | Convert an identifier to a relative 'FilePath'
--
2011-05-24 09:58:13 +00:00
toFilePath :: Identifier a -> FilePath
toFilePath = identifierPath
2011-04-11 16:10:45 +00:00
-- | Set the identifier group for some identifier
--
2011-05-24 09:58:13 +00:00
setGroup :: Maybe String -> Identifier a -> Identifier a
2011-04-11 19:57:33 +00:00
setGroup g (Identifier _ p) = Identifier g p