|
1 | 1 | {-# LANGUAGE OverloadedStrings #-}
|
2 | 2 |
|
3 |
| -import Control.Monad (replicateM) |
| 3 | +import Control.Monad (forM_, replicateM) |
4 | 4 | import Data.Maybe (fromMaybe)
|
5 | 5 | import Data.Monoid
|
| 6 | +import Data.String (fromString) |
6 | 7 | import Hakyll
|
7 | 8 | import Main.Utf8 (withUtf8)
|
8 | 9 | import System.FilePath
|
@@ -75,63 +76,73 @@ main = withUtf8 . hakyllWith cfg $ do
|
75 | 76 | match "bip39/*" $ do
|
76 | 77 | route idRoute
|
77 | 78 | compile copyFileCompiler
|
78 |
| - create ["bip39/calculator.html"] $ do |
79 |
| - let defCtx = mkStyleCtx Formal |
80 |
| - route idRoute |
81 |
| - compile $ do |
82 |
| - let idxs items label = |
83 |
| - listField |
84 |
| - label |
85 |
| - ( field "idx" (pure . itemBody) |
86 |
| - <> defCtx |
87 |
| - ) |
88 |
| - ( do |
89 |
| - xs <- mapM (makeItem . ("\8470" <>) . show) items |
90 |
| - x <- makeItem mempty |
91 |
| - pure $ x : xs |
92 |
| - ) |
93 |
| - let rows top label = |
94 |
| - listField |
95 |
| - label |
96 |
| - ( listFieldWith |
97 |
| - "cols" |
98 |
| - (field "col" (pure . itemBody)) |
99 |
| - ( \item -> do |
100 |
| - let (idx, raw) = itemBody item |
101 |
| - h <- |
102 |
| - makeItem . (\x -> "<b>" <> x <> "</b>") $ |
103 |
| - if idx <= 11 |
104 |
| - then "bit " <> show idx |
105 |
| - else raw |
106 |
| - xs <- |
107 |
| - replicateM 11 . makeItem $ |
108 |
| - if idx <= 11 |
109 |
| - then raw |
110 |
| - else mempty |
111 |
| - t <- |
112 |
| - makeItem $ |
113 |
| - if (top || idx < 4) && idx <= 11 |
114 |
| - then raw |
115 |
| - else mempty |
116 |
| - pure $ [h] <> xs <> [t] |
117 |
| - ) |
118 |
| - ) |
119 |
| - ( mapM makeItem |
120 |
| - . zip [1 ..] |
121 |
| - . (<> ["sum=", "sum+1=", "word="]) |
122 |
| - $ fmap (show . (2 ^)) [0 .. 10] |
123 |
| - ) |
124 |
| - let ctx = |
125 |
| - idxs [1 .. 12] "idxs-top" |
126 |
| - <> idxs [13 .. 24] "idxs-bottom" |
127 |
| - <> rows True "rows-top" |
128 |
| - <> rows False "rows-bottom" |
129 |
| - <> constField "title" "BIP39 Dice Calculator" |
130 |
| - <> defCtx |
131 |
| - makeItem "" |
132 |
| - >>= loadAndApplyTemplate "templates/bip39-dice-calculator.html" ctx |
133 |
| - >>= loadAndApplyTemplate "templates/default.html" ctx |
134 |
| - >>= relativizeUrls |
| 79 | + forM_ colors $ \mcolor -> do |
| 80 | + let color = fromMaybe "black" mcolor |
| 81 | + let name = |
| 82 | + "bip39/calculator" |
| 83 | + <> maybe mempty ("-" <>) mcolor |
| 84 | + <> ".html" |
| 85 | + create [fromString name] $ do |
| 86 | + let defCtx = |
| 87 | + mkStyleCtx Formal |
| 88 | + <> constField "table-color" color |
| 89 | + route idRoute |
| 90 | + compile $ do |
| 91 | + let idxs items label = |
| 92 | + listField |
| 93 | + label |
| 94 | + ( field "idx" (pure . itemBody) |
| 95 | + <> defCtx |
| 96 | + ) |
| 97 | + ( do |
| 98 | + xs <- mapM (makeItem . ("\8470" <>) . show) items |
| 99 | + x <- makeItem mempty |
| 100 | + pure $ x : xs |
| 101 | + ) |
| 102 | + let rows top label = |
| 103 | + listField |
| 104 | + label |
| 105 | + ( listFieldWith |
| 106 | + "cols" |
| 107 | + ( field "col" (pure . itemBody) |
| 108 | + <> defCtx |
| 109 | + ) |
| 110 | + ( \item -> do |
| 111 | + let (idx, raw) = itemBody item |
| 112 | + h <- |
| 113 | + makeItem . (\x -> "<b>" <> x <> "</b>") $ |
| 114 | + if idx <= 11 |
| 115 | + then "bit " <> show idx |
| 116 | + else raw |
| 117 | + xs <- |
| 118 | + replicateM 11 . makeItem $ |
| 119 | + if idx <= 11 |
| 120 | + then raw |
| 121 | + else mempty |
| 122 | + t <- |
| 123 | + makeItem $ |
| 124 | + if (top || idx < 4) && idx <= 11 |
| 125 | + then raw |
| 126 | + else mempty |
| 127 | + pure $ [h] <> xs <> [t] |
| 128 | + ) |
| 129 | + ) |
| 130 | + ( mapM makeItem |
| 131 | + . zip [1 ..] |
| 132 | + . (<> ["sum=", "sum+1=", "word="]) |
| 133 | + $ fmap (show . (2 ^)) [0 .. 10] |
| 134 | + ) |
| 135 | + let ctx = |
| 136 | + idxs [1 .. 12] "idxs-top" |
| 137 | + <> idxs [13 .. 24] "idxs-bottom" |
| 138 | + <> rows True "rows-top" |
| 139 | + <> rows False "rows-bottom" |
| 140 | + <> constField "title" "BIP39 Dice Calculator" |
| 141 | + <> defCtx |
| 142 | + makeItem "" |
| 143 | + >>= loadAndApplyTemplate "templates/bip39-dice-calculator.html" ctx |
| 144 | + >>= loadAndApplyTemplate "templates/default.html" ctx |
| 145 | + >>= relativizeUrls |
135 | 146 | match "templates/*" $ compile templateBodyCompiler
|
136 | 147 | match "license.markdown" $ compile pandocCompiler
|
137 | 148 | match "index/*.markdown" $ compile pandocCompiler
|
@@ -207,3 +218,13 @@ mkStyleCtx style =
|
207 | 218 | constField "formal" "true"
|
208 | 219 | <> constField "color" "white"
|
209 | 220 | <> defaultContext
|
| 221 | + |
| 222 | +colors :: [Maybe String] |
| 223 | +colors = |
| 224 | + [ Nothing, |
| 225 | + Just "red", |
| 226 | + Just "green", |
| 227 | + Just "blue", |
| 228 | + Just "cyan", |
| 229 | + Just "magenta" |
| 230 | + ] |
0 commit comments