Skip to content

Commit

Permalink
Fix Unicode file embedding: embedStringFile → embedFileUtf8
Browse files Browse the repository at this point in the history
  • Loading branch information
f-f committed Dec 20, 2018
1 parent 321cada commit 715c1e7
Show file tree
Hide file tree
Showing 3 changed files with 30 additions and 6 deletions.
22 changes: 22 additions & 0 deletions app/Spago/TH.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
{-# LANGUAGE TemplateHaskell #-}

module Spago.TH
( embedFileUtf8
) where

import Data.FileEmbed
import Data.Text.Encoding as LT
import Language.Haskell.TH.Syntax (Exp, Q)


-- | This is here so that we can embed files as Utf8 Text.
-- The reason for that is that since we have unicode Dhall files,
-- if you compile on a non-unicode system you'll get weirdly encoded stuff.
--
-- TL;DR: don't use embedStringFile.
--
-- This comes from:
-- https://github.com/snoyberg/file-embed/issues/27#issuecomment-411694346
embedFileUtf8 :: FilePath -> Q Exp
embedFileUtf8 filePath =
[| LT.decodeUtf8 $(makeRelativeToProject filePath >>= embedFile) |]
13 changes: 7 additions & 6 deletions app/Spago/Templates.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,27 +3,28 @@
module Spago.Templates where

import Data.Aeson.Encode.Pretty
import Data.FileEmbed
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT

import PscPackage.Types (PscPackage (..))
import Spago.TH (embedFileUtf8)


packagesDhall :: T.Text
packagesDhall = $(embedStringFile "templates/packages.dhall")
packagesDhall = $(embedFileUtf8 "templates/packages.dhall")

spagoDhall :: T.Text
spagoDhall = $(embedStringFile "templates/spago.dhall")
spagoDhall = $(embedFileUtf8 "templates/spago.dhall")

srcMain :: T.Text
srcMain = $(embedStringFile "templates/srcMain.purs")
srcMain = $(embedFileUtf8 "templates/srcMain.purs")

testMain :: T.Text
testMain = $(embedStringFile "templates/testMain.purs")
testMain = $(embedFileUtf8 "templates/testMain.purs")

gitignore :: T.Text
gitignore = $(embedStringFile "templates/gitignore")
gitignore = $(embedFileUtf8 "templates/gitignore")

encodePscPackage :: PscPackage -> T.Text
encodePscPackage = LT.toStrict . LT.decodeUtf8 . encodePretty
Expand Down
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ dependencies:
- prettyprinter
- async-pool
- process
- template-haskell

executables:
spago:
Expand Down

0 comments on commit 715c1e7

Please sign in to comment.