--------------------------------------------------------------------------------
-- | An identifier is a type used to uniquely name an item. An identifier
-- is similar to a file path, but can contain additional details (e.g. 
-- item's version). Examples of identifiers are:
--
-- * @posts/foo.markdown@
--
-- * @index@
--
-- * @error/404@
--
-- See 'Identifier' for details.

{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Identifier
    ( Identifier
    , fromFilePath
    , toFilePath
    , identifierVersion
    , setVersion
    ) where


--------------------------------------------------------------------------------
import           Control.DeepSeq     (NFData (..))
import           Data.List           (intercalate)
import           System.FilePath     (dropTrailingPathSeparator, splitPath,
                                      pathSeparator, normalise)


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


--------------------------------------------------------------------------------
{- | A key data type to identify a compiled 'Hakyll.Core.Item.Item' in the 'Hakyll.Core.Store.Store'.
Conceptually, it's a combination of a file path and a version name.
The version is used only when a file is
compiled within a rule using the 'version' wrapper function
(the same source file
can be compiled into several items in the store, so the version exists to distinguish
them).
Use functions like 'fromFilePath', 'setVersion', 'Hakyll.Core.Metadata.getMatches' to build an 'Identifier'.

=== __Usage Examples__
Normally, compiled items are saved to the store by 'Hakyll.Core.Rules.Rules' with an automatic, implicit identifier
and loaded from the store by the user in another rule with a manual, explicit identifier.

__Identifiers when using match__.
Using 'Hakyll.Core.Rules.match' builds an implicit identifier that corresponds to the expanded, relative path
of the source file on disk (relative to the project directory configured
with 'Hakyll.Core.Configuration.providerDirectory'):

@
-- e.g. file on disk: 'posts\/hakyll.md'
match "posts/*" $ do                                          -- saved with implicit identifier 'posts\/hakyll.md'
    compile pandocCompiler

match "about/*" $ do
    compile $ do
        compiledPost <- load (fromFilePath "posts/hakyll.md") -- load with explicit identifier
        ...
@
Normally, the identifier is only explicitly created to pass to one of the 'Hakyll.Core.Compiler.load' functions.

__Identifiers when using create__.
Using 'Hakyll.Core.Rules.create' (thereby inventing a file path with no underlying file on disk)
builds an implicit identifier that corresponds to the invented file path:

@
create ["index.html"] $ do                                -- saved with implicit identifier 'index.html'
    compile $ makeItem ("Hello world" :: String)

match "about/*" $ do
    compile $ do
        compiledIndex <- load (fromFilePath "index.html") -- load with an explicit identifier
        ...
@

__Identifiers when using versions__.
With 'Hakyll.Core.Rules.version' the same file can be compiled into several items in the store.
A version name is needed to distinguish them:

@
-- e.g. file on disk: 'posts\/hakyll.md'
match "posts/*" $ do                              -- saved with implicit identifier ('posts\/hakyll.md', no-version)
    compile pandocCompiler

match "posts/*" $ version "raw" $ do              -- saved with implicit identifier ('posts\/hakyll.md', version 'raw')
    compile getResourceBody

match "about/*" $ do
    compile $ do
        compiledPost <- load (fromFilePath "posts/hakyll.md")                      -- load no-version version
        rawPost <- load . setVersion (Just "raw") $ fromFilePath "posts/hakyll.md" -- load version 'raw'
    ...
@
Use 'setVersion' to set (or replace) the version of an identifier like @fromFilePath "posts/hakyll.md"@.
-}
data Identifier = Identifier
    { Identifier -> Maybe String
identifierVersion :: Maybe String
    , Identifier -> String
identifierPath    :: String
    } deriving (Identifier -> Identifier -> Bool
(Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool) -> Eq Identifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identifier -> Identifier -> Bool
$c/= :: Identifier -> Identifier -> Bool
== :: Identifier -> Identifier -> Bool
$c== :: Identifier -> Identifier -> Bool
Eq, Eq Identifier
Eq Identifier
-> (Identifier -> Identifier -> Ordering)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Identifier)
-> (Identifier -> Identifier -> Identifier)
-> Ord Identifier
Identifier -> Identifier -> Bool
Identifier -> Identifier -> Ordering
Identifier -> Identifier -> Identifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Identifier -> Identifier -> Identifier
$cmin :: Identifier -> Identifier -> Identifier
max :: Identifier -> Identifier -> Identifier
$cmax :: Identifier -> Identifier -> Identifier
>= :: Identifier -> Identifier -> Bool
$c>= :: Identifier -> Identifier -> Bool
> :: Identifier -> Identifier -> Bool
$c> :: Identifier -> Identifier -> Bool
<= :: Identifier -> Identifier -> Bool
$c<= :: Identifier -> Identifier -> Bool
< :: Identifier -> Identifier -> Bool
$c< :: Identifier -> Identifier -> Bool
compare :: Identifier -> Identifier -> Ordering
$ccompare :: Identifier -> Identifier -> Ordering
$cp1Ord :: Eq Identifier
Ord, Typeable)


--------------------------------------------------------------------------------
instance Binary Identifier where
    put :: Identifier -> Put
put (Identifier Maybe String
v String
p) = Maybe String -> Put
forall t. Binary t => t -> Put
put Maybe String
v Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Put
forall t. Binary t => t -> Put
put String
p
    get :: Get Identifier
get = Maybe String -> String -> Identifier
Identifier (Maybe String -> String -> Identifier)
-> Get (Maybe String) -> Get (String -> Identifier)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe String)
forall t. Binary t => Get t
get Get (String -> Identifier) -> Get String -> Get Identifier
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get String
forall t. Binary t => Get t
get


--------------------------------------------------------------------------------
instance IsString Identifier where
    fromString :: String -> Identifier
fromString = String -> Identifier
fromFilePath


--------------------------------------------------------------------------------
instance NFData Identifier where
    rnf :: Identifier -> ()
rnf (Identifier Maybe String
v String
p) = Maybe String -> ()
forall a. NFData a => a -> ()
rnf Maybe String
v () -> () -> ()
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
p () -> () -> ()
`seq` ()


--------------------------------------------------------------------------------
instance Show Identifier where
    show :: Identifier -> String
show Identifier
i = case Identifier -> Maybe String
identifierVersion Identifier
i of
        Maybe String
Nothing -> Identifier -> String
toFilePath Identifier
i
        Just String
v  -> Identifier -> String
toFilePath Identifier
i String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"


--------------------------------------------------------------------------------
{- | Parse an identifier from a file path string. For example, 

@
-- e.g. file on disk: 'posts\/hakyll.md'
match "posts/*" $ do                                          -- saved with implicit identifier 'posts\/hakyll.md'
    compile pandocCompiler

match "about/*" $ do
    compile $ do
        compiledPost <- load (fromFilePath "posts/hakyll.md") -- load with explicit identifier
        ...
@
-}
fromFilePath :: FilePath -> Identifier
fromFilePath :: String -> Identifier
fromFilePath = Maybe String -> String -> Identifier
Identifier Maybe String
forall a. Maybe a
Nothing (String -> Identifier) -> ShowS -> String -> Identifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
normalise


--------------------------------------------------------------------------------
-- | Convert an identifier back to a relative 'FilePath'.
toFilePath :: Identifier -> FilePath
toFilePath :: Identifier -> String
toFilePath = ShowS
normalise ShowS -> (Identifier -> String) -> Identifier -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identifier -> String
identifierPath


--------------------------------------------------------------------------------
{- | Set or override the version of an identifier in order to specify which version of an 'Hakyll.Core.Item.Item' 
to 'Hakyll.Core.Compiler.load' from the 'Hakyll.Core.Store.Store'. For example,

@
match "posts/*" $ version "raw" $ do              -- saved with implicit identifier ('posts\/hakyll.md', version 'raw')
    compile getResourceBody

match "about/*" $ do
    compile $ do
        rawPost <- load . setVersion (Just "raw") $ fromFilePath "posts/hakyll.md" -- load version 'raw'
        ...
@
-}
setVersion :: Maybe String -> Identifier -> Identifier
setVersion :: Maybe String -> Identifier -> Identifier
setVersion Maybe String
v Identifier
i = Identifier
i {identifierVersion :: Maybe String
identifierVersion = Maybe String
v}