summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Identifier.hs
blob: ade040538957cc9f1f8a2d13502291247cea7161 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
-- | 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@
--
-- 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.
--
-- An `Identifier` carries the type of the value it identifies. This basically
-- means that an @Identifier (Page String)@ refers to a page.
--
-- It is a phantom type parameter, meaning you can safely change this if you
-- know what you are doing. You can change the type using the 'castIdentifier'
-- function.
--
-- If the @a@ type is not known, Hakyll traditionally uses @Identifier ()@.
--
{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-}
module Hakyll.Core.Identifier
    ( Identifier (..)
    , castIdentifier
    , parseIdentifier
    , fromFilePath
    , toFilePath
    , setGroup
    ) where

import Control.Applicative ((<$>), (<*>))
import Control.DeepSeq (NFData (..))
import Control.Monad (mplus)
import Data.Monoid (Monoid, mempty, mappend)
import Data.List (intercalate)
import System.FilePath (dropTrailingPathSeparator, splitPath)

import Data.Binary (Binary, get, put)
import GHC.Exts (IsString, fromString)
import Data.Typeable (Typeable)

-- | An identifier used to uniquely identify a value
--
data Identifier a = Identifier
    { identifierGroup :: Maybe String
    , identifierPath  :: String
    } deriving (Eq, Ord, Typeable)

instance Monoid (Identifier a) where
    mempty = Identifier Nothing ""
    Identifier g1 p1 `mappend` Identifier g2 p2 =
        Identifier (g1 `mplus` g2) (p1 `mappend` p2)

instance Binary (Identifier a) where
    put (Identifier g p) = put g >> put p
    get = Identifier <$> get <*> get

instance Show (Identifier a) where
    show i@(Identifier Nothing _)  = toFilePath i
    show i@(Identifier (Just g) _) = toFilePath i ++ " (" ++ g ++ ")"

instance IsString (Identifier a) where
    fromString = parseIdentifier

instance NFData (Identifier a) where
    rnf (Identifier g p) = rnf g `seq` rnf p `seq` ()

-- | Discard the phantom type parameter of an identifier
--
castIdentifier :: Identifier a -> Identifier b
castIdentifier (Identifier g p) = Identifier g p
{-# INLINE castIdentifier #-}


--------------------------------------------------------------------------------
-- | Parse an identifier from a string
parseIdentifier :: String -> Identifier a
parseIdentifier = Identifier Nothing .
    intercalate "/" . filter (not . null) . split'
  where
    split' = map dropTrailingPathSeparator . splitPath


--------------------------------------------------------------------------------
-- | Create an identifier from a filepath
fromFilePath :: FilePath -> Identifier a
fromFilePath = parseIdentifier


--------------------------------------------------------------------------------
-- | Convert an identifier to a relative 'FilePath'
toFilePath :: Identifier a -> FilePath
toFilePath = identifierPath

-- | Set the identifier group for some identifier
--
setGroup :: Maybe String -> Identifier a -> Identifier a
setGroup g (Identifier _ p) = Identifier g p