summaryrefslogtreecommitdiff
path: root/src/Hakyll/Main.hs
blob: e0f5b9333114f0b8fec97529e1c6874ce1f2d3f0 (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
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
-- | Module providing the main hakyll function and command-line argument parsing
--
{-# LANGUAGE CPP #-}
module Hakyll.Main
    ( hakyll
    , hakyllWith
    ) where

import Control.Monad (when)
import System.Directory (doesDirectoryExist, removeDirectoryRecursive)
import System.Environment (getProgName, getArgs)
import System.Process (system)

import Hakyll.Core.Configuration
import Hakyll.Core.Identifier
import Hakyll.Core.Runtime
import Hakyll.Core.Rules

#ifdef PREVIEW_SERVER
import Control.Applicative ((<$>))
import Control.Concurrent (forkIO)
import qualified Data.Set as S

import Hakyll.Core.Rules.Internal
import Hakyll.Web.Preview.Poll
import Hakyll.Web.Preview.Server
#endif

-- | This usualy is the function with which the user runs the hakyll compiler
--
hakyll :: Rules a -> IO ()
hakyll = hakyllWith defaultConfiguration

-- | A variant of 'hakyll' which allows the user to specify a custom
-- configuration
--
hakyllWith :: Configuration -> Rules a -> IO ()
hakyllWith conf rules = do
    args <- getArgs
    case args of
        ["build"]      -> build conf rules
        ["clean"]      -> clean conf
        ["help"]       -> help
        ["preview"]    -> preview conf rules 8000
        ["preview", p] -> preview conf rules (read p)
        ["rebuild"]    -> rebuild conf rules
        ["server"]     -> server conf 8000
        ["server", p]  -> server conf (read p)
        ["deploy"]     -> deploy conf
        _              -> help

-- | Build the site
--
build :: Configuration -> Rules a -> IO ()
build conf rules = do
    _ <- run conf rules
    return ()

-- | Remove the output directories
--
clean :: Configuration -> IO ()
clean conf = do
    remove $ destinationDirectory conf
    remove $ storeDirectory conf
  where
    remove dir = do
        putStrLn $ "Removing " ++ dir ++ "..."
        exists <- doesDirectoryExist dir
        when exists $ removeDirectoryRecursive dir

-- | Show usage information.
--
help :: IO ()
help = do
    name <- getProgName
    mapM_ putStrLn
        [ "ABOUT"
        , ""
        , "This is a Hakyll site generator program. You should always"
        , "run it from the project root directory."
        , ""
        , "USAGE"
        , ""
        , name ++ " build           Generate the site"
        , name ++ " clean           Clean up and remove cache"
        , name ++ " help            Show this message"
        , name ++ " preview [port]  Run a server and autocompile"
        , name ++ " rebuild         Clean up and build again"
        , name ++ " server [port]   Run a local test server"
        , name ++ " deploy          Upload/deploy your site"
        , ""
        ]

#ifndef PREVIEW_SERVER
    previewServerDisabled
#endif

-- | Preview the site
--
preview :: Configuration -> Rules a -> Int -> IO ()
#ifdef PREVIEW_SERVER
preview conf rules port = do
    -- Fork a thread polling for changes
    _ <- forkIO $ previewPoll conf update

    -- Run the server in the main thread
    server conf port
  where
    update = map toFilePath . S.toList . rulesResources <$> run conf rules
#else
preview _ _ _ = previewServerDisabled
#endif

-- | Rebuild the site
--
rebuild :: Configuration -> Rules a -> IO ()
rebuild conf rules = do
    clean conf
    build conf rules

-- | Start a server
--
server :: Configuration -> Int -> IO ()
#ifdef PREVIEW_SERVER
server conf port = do
    let destination = destinationDirectory conf
    staticServer destination preServeHook port
  where
    preServeHook _ = return ()
#else
server _ _ = previewServerDisabled
#endif

-- | Upload the site
--
deploy :: Configuration -> IO ()
deploy conf = do
    _ <- system $ deployCommand conf
    return ()

-- | Print a warning message about the preview serving not being enabled
--
#ifndef PREVIEW_SERVER
previewServerDisabled :: IO ()
previewServerDisabled =
    mapM_ putStrLn
        [ "PREVIEW SERVER"
        , ""
        , "The preview server is not enabled in the version of Hakyll. To"
        , "enable it, set the flag to True and recompile Hakyll."
        , "Alternatively, use an external tool to serve your site directory."
        ]
#endif