-
Notifications
You must be signed in to change notification settings - Fork 5
/
Build.hs
executable file
·230 lines (202 loc) · 7.17 KB
/
Build.hs
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
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
#!/usr/bin/env cabal
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE BlockArguments #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}
{-# OPTIONS_GHC -Wno-unused-imports #-}
{- cabal:
build-depends:
base >= 4.16,
dhall >= 1.41,
directory >= 1.3.7.0,
extra >= 1.7.4,
language-javascript >= 0.7.1.0,
pretty-simple >= 4.1,
shake >= 0.19.1,
shake-dhall >= 0.1.0.0,
text >= 1.2.3,
-}
module Main (main) where
import Control.Exception.Extra
import Control.Monad
import Control.Monad.Extra
import Data.Bool
import Data.Either.Extra
import Data.Foldable
import Data.Function
import Data.List
import Data.Monoid.Extra
import System.Console.GetOpt
import System.IO.Error
import System.Info.Extra
import Data.Text (Text, pack)
import Data.Text.IO qualified as T
import Data.Text.Lazy.IO qualified as TL
import Dhall.Core qualified as Dhall
import Dhall.Import qualified as Dhall
import Dhall.Parser qualified as Dhall
import Dhall.TypeCheck qualified as Dhall
import GHC.IO.Encoding (setLocaleEncoding, utf8)
import Language.JavaScript.Parser qualified as JS
import Language.JavaScript.Process.Minify qualified as JS
import System.Directory qualified as Dir
import Development.Shake
import Development.Shake.Dhall
import Development.Shake.FilePath
import Text.Pretty.Simple
data Args
= Target String
| Compiler String
deriving (Show)
optDescrs :: [OptDescr (Either String Args)]
optDescrs =
[ Option
[]
["target"]
(OptArg (maybeToEither "no arg" . fmap Target) "triple")
"Cross compile. Expects a suitably-prefixed `cabal` to be available."
, Option
['w']
[]
(OptArg (maybeToEither "no arg" . fmap Compiler) "path")
"Path to GHC binary to use."
]
main :: IO ()
main = do
setLocaleEncoding utf8
shakeArgsWith shakeOptions{shakeColor = True, shakeThreads = 0} optDescrs \args wanted ->
pure $ pure $ uncurry (rules wanted) case args of
[Target s] -> ("ghc", Just s)
[Compiler s] -> (s, Nothing)
[] -> ("ghc", Nothing)
_ -> error "incompatible args"
rules :: [String] -> String -> Maybe String -> Rules ()
rules wanted ghc maybeTarget = do
let cabal = maybe "cabal" (<> "-cabal") maybeTarget
qualify = maybe id (flip (</>)) maybeTarget
buildDirBase = ".build"
buildDir = qualify buildDirBase
hsBuildDir = buildDir </> "hs"
distDir = qualify "dist"
monpad = distDir </> "monpad" <.> exe
monpadDebug = distDir </> "monpad-debug" <.> exe
want case wanted of
[] -> [monpad]
_ -> wanted
forM_ copiedAssets \(file, copy) ->
copy %> \_ -> do
putInfo $ "Copying " <> file <> " to " <> copy
bool copyFileChanged minifyFileJS (takeExtension file == ".js") file copy
let haskell path flags = do
need assets
-- TODO shouldn't need to exclude `dist-newstyle` but it can still end up being used for `cabal repl` etc.
-- due to https://github.com/haskell/cabal/issues/5271
needDirExcept (hsDir </> "dist-newstyle") hsDir
let args =
[ "exe:monpad"
, "--flags=" <> flags
, "--builddir=" <> (".." </> hsBuildDir)
, "-w" <> ghc
]
cmd_
(Cwd hsDir)
cabal
"build"
args
bins <-
lines . fromStdout
<$> cmd
(Cwd hsDir)
cabal
"list-bin"
args
case bins of
[] -> error "No matches"
[path'] -> copyFileChanged path' path
fs -> error $ "Multiple matches: " <> intercalate ", " fs
monpad %> \_ -> do
haskell monpad "release"
let elm optimise = do
needDirExcept elmBuildDir elmDir
out <- liftIO $ (</> "monpad-elm.js") <$> Dir.getTemporaryDirectory
cmd_ (Cwd "elm") "elm make src/Main.elm --output" out (mwhen optimise "--optimize")
bool (liftIO .: Dir.copyFile) minifyFileJS optimise out elmJS
elmJS %> \_ -> elm True
distDir </> "dhall" </> "*" %> \out -> do
let in' = "dhall" </> takeFileName out
needDhall [in']
putInfo $ "Resolving imports in: " <> out
liftIO $ do
c <- T.readFile in'
expr <-
Dhall.throws . Dhall.exprFromText in' $
pack "(./lib/map-layout.dhall).to" <> osName <> pack " " <> bracketed c
-- TODO huge due to https://github.com/dhall-lang/dhall-haskell/issues/2116
resolvedExpression <- Dhall.loadRelativeTo (takeDirectory in') Dhall.UseSemanticCache expr
_ <- Dhall.throws $ Dhall.typeOf resolvedExpression
T.writeFile out $ Dhall.pretty resolvedExpression
-- unoptimised, and needs to be run from a directory containing `rsc`, with all the JS/CSS etc. assets
"debug" ~> do
haskell monpadDebug ""
rscs <- liftIO $ Dir.listDirectory rscDir
for_ rscs $ \r -> copyFileChanged (rscDir </> r) (distDir </> rsc </> r)
"elm" ~> need [elmJS]
"elm-debug" ~> elm False
"dhall" ~> do
need . map ((distDir </> "dhall") </>) =<< getDirectoryFiles "dhall" ["*"]
"assets" ~> need assets
"clean" ~> do
rmr shakeDir
rmr rscDir
rmr distDir
rmr buildDir
rmr elmBuildDir
{- Constants -}
shakeDir, rsc, rscDir, hsDir, elmDir, elmBuildDir, elmJS :: FilePath
shakeDir = ".shake"
rsc = "rsc"
rscDir = hsDir </> rsc
hsDir = "haskell"
elmDir = "elm"
elmBuildDir = elmDir </> "elm-stuff"
elmJS = rscDir </> "elm" <.> "js"
copiedAssets :: [(FilePath, FilePath)]
copiedAssets =
[ (file, rscDir </> takeFileName file)
| file <-
[ "dist" </> "dhall" </> "default.dhall"
, "js" </> "main.js"
, "css" </> "common.css"
, "css" </> "login.css"
, "css" </> "app.css"
]
]
assets :: [FilePath]
assets = elmJS : map snd copiedAssets
osName :: Text
osName = pack case os of
"mingw32" -> "Windows"
"darwin" -> "Mac"
"linux" -> "Linux"
_ -> "unknown"
{- Util -}
-- | `rm -r`
rmr :: FilePath -> Action ()
rmr dir = liftIO $ removeFiles dir ["//*"]
-- | Need all files in 'dir' except those in 'except'
needDirExcept :: FilePath -> FilePath -> Action ()
needDirExcept except dir =
need . filter (not . (isPrefixOf `on` splitDirectories) except) =<< getDirectoryFiles "" [dir <//> "*"]
minifyFileJS :: FilePath -> FilePath -> Action ()
minifyFileJS in_ out = do
need [in_]
contents <- liftIO $ readFile in_
cmd_ "closure-compiler" in_ "--js_output_file" out `actionCatch` \(e :: IOError) -> do
putInfo $ "Failed to run external minifier, trying Haskell version: " <> show e
case JS.parse contents in_ of
Left s -> error $ "Failed to parse " <> in_ <> " as JavaScript:\n" <> s
Right ast -> liftIO $ TL.writeFile out $ JS.renderToText $ JS.minifyJS ast
bracketed :: Text -> Text
bracketed t = pack "(" <> t <> pack ")"
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(.:) = (.) . (.)