Skip to content

Commit 9de64d8

Browse files
authored
Explicitly set local encoding to UTF-8 in site.hs (#255)
This change makes sure that the site executable *always* expects UTF-8, regardless of any locale environment variables. This should avoid problems like #29 and #249 in a more robust way than trying to set the right environment variables in `buildAndWatch` or `shell.nix`. The diff ended up a bit noisy because of indentation changes; the key change was adding `Encoding.setLocaleEncoding Encoding.utf8` to the beginning of `main`. I tested this by reproducing the Unicode error (using `nix-shell --pure`) and checking that the Haskell code change fixes the problem.
1 parent f36b210 commit 9de64d8

File tree

3 files changed

+52
-53
lines changed

3 files changed

+52
-53
lines changed

buildAndWatch

-1
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@ function buildAndWatchWithNix() {
1212
exit 1
1313
fi
1414

15-
export LC_ALL=C.UTF-8 # fix locale error with Hakyll (see #29)
1615
nix-build -A builder && \
1716
./result/bin/haskell-org-site clean && \
1817
./result/bin/haskell-org-site build && \

builder/site.hs

+52-49
Original file line numberDiff line numberDiff line change
@@ -1,68 +1,71 @@
11
--------------------------------------------------------------------------------
2-
{-# LANGUAGE TypeApplications #-}
32
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE TypeApplications #-}
44
import Data.Aeson
55
import qualified Data.ByteString.Lazy as BL
66
import Data.Monoid ((<>))
77
import Data.Time.Calendar
88
import Data.Time.Clock
9+
import qualified GHC.IO.Encoding as Encoding
910
import Hakyll
1011
import Hakyll.Core.Compiler
1112
import Hakyll.Core.Compiler.Internal
1213
import Hakyll.Core.Provider
1314
import System.FilePath.Posix
1415
import Testimonial
1516

16-
1717
--------------------------------------------------------------------------------
1818
main :: IO ()
19-
main = mkContext >>= \ctx -> hakyllWith configuration $ do
20-
match "testimonials/logos/*" $ do
21-
route idRoute
22-
compile copyFileCompiler
23-
24-
match "testimonials/*.yaml" $ do
25-
compile parseTestimonialCompiler
26-
27-
create ["testimonials.json"] $ do
28-
route idRoute
29-
compile $ do
30-
testimonials <- loadAll @Testimonial "testimonials/*.yaml"
31-
item <- (makeItem . BL.unpack . encode . map itemBody) testimonials
32-
saveSnapshot "_final" item
33-
pure item
34-
35-
match "img/*" $ do
36-
route idRoute
37-
compile copyFileCompiler
38-
39-
match "css/*" $ do
40-
route idRoute
41-
compile compressCssCompiler
42-
43-
match "js/*" $ do
44-
route idRoute
45-
compile copyFileCompiler
46-
47-
match "index.html" $ do
48-
route idRoute
49-
compile $ do
50-
testimonials <- loadAll @Testimonial "testimonials/*.yaml"
51-
let
52-
indexCtx = listField "testimonials" testimonialContext (pure testimonials) `mappend`
53-
ctx
54-
defCompiler indexCtx
55-
56-
match ("**/*.markdown" .||. "*.markdown") $ do
57-
route cleanRoute
58-
compile $ mdCompiler ctx
59-
60-
match "*.pdf" $ do
61-
route idRoute
62-
compile copyFileCompiler
63-
64-
match "templates/*" $
65-
compile templateCompiler
19+
main = do
20+
Encoding.setLocaleEncoding Encoding.utf8
21+
ctx <- mkContext
22+
hakyllWith configuration $ do
23+
match "testimonials/logos/*" $ do
24+
route idRoute
25+
compile copyFileCompiler
26+
27+
match "testimonials/*.yaml" $ do
28+
compile parseTestimonialCompiler
29+
30+
create ["testimonials.json"] $ do
31+
route idRoute
32+
compile $ do
33+
testimonials <- loadAll @Testimonial "testimonials/*.yaml"
34+
item <- (makeItem . BL.unpack . encode . map itemBody) testimonials
35+
saveSnapshot "_final" item
36+
pure item
37+
38+
match "img/*" $ do
39+
route idRoute
40+
compile copyFileCompiler
41+
42+
match "css/*" $ do
43+
route idRoute
44+
compile compressCssCompiler
45+
46+
match "js/*" $ do
47+
route idRoute
48+
compile copyFileCompiler
49+
50+
match "index.html" $ do
51+
route idRoute
52+
compile $ do
53+
testimonials <- loadAll @Testimonial "testimonials/*.yaml"
54+
let
55+
indexCtx = listField "testimonials" testimonialContext (pure testimonials) `mappend`
56+
ctx
57+
defCompiler indexCtx
58+
59+
match ("**/*.markdown" .||. "*.markdown") $ do
60+
route cleanRoute
61+
compile $ mdCompiler ctx
62+
63+
match "*.pdf" $ do
64+
route idRoute
65+
compile copyFileCompiler
66+
67+
match "templates/*" $
68+
compile templateCompiler
6669

6770

6871
configuration :: Configuration

default.nix

-3
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,6 @@ let
1818
] ./.;
1919
buildInputs = [ builder pkgs.linkchecker ];
2020

21-
LOCALE_ARCHIVE = "${pkgs.glibcLocales}/lib/locale/locale-archive";
22-
LC_ALL = "C.UTF-8";
23-
2421
buildPhase = ''
2522
${builder}/bin/haskell-org-site build
2623
'';

0 commit comments

Comments
 (0)