Cosmetics
[llpp.git] / Build.hs
blob95dc6be11e32a51ea639fcaf2430f769af196c51
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
3 import Data.List
4 import System.Exit
5 import Control.Monad
6 import Control.Concurrent.MVar
7 import Development.Shake
8 import Development.Shake.Util
9 import Development.Shake.Classes
10 import Development.Shake.FilePath
12 newtype OcamlOrdOracle = OcamlOrdOracle String
13 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
14 newtype OcamlOrdOracleN = OcamlOrdOracleN String
15 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
16 newtype OcamlCmdLineOracle = OcamlCmdLineOracle String
17 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
18 newtype OcamlCmdLineOracleN = OcamlCmdLineOracleN String
19 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
20 newtype CCmdLineOracle = CCmdLineOracle String
21 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
22 newtype GitDescribeOracle = GitDescribeOracle ()
23 deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
25 outdir = "build"
26 mudir = "mupdf"
27 inOutDir s = outdir </> s
29 ocamlc = "ocamlc.opt"
30 ocamlopt = "ocamlopt.opt"
31 ocamldep = "ocamldep.opt"
32 ocamlflags = "-warn-error +a -w +a -g -safe-string"
33 ocamlflagstbl = [("main.cmo", ("-I lablGL", "sed -f pp.sed"))
34 ,("config.cmo", ("-I lablGL", ""))
36 ocamlflagstbln = [("main.cmx", ("-I lablGL", "sed -f pp.sed"))
37 ,("config.cmx", ("-I lablGL", ""))
39 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
40 \ -g -std=c99 -pedantic-errors\
41 \ -Wunused-parameter -Wsign-compare -Wshadow"
42 cflagstbl =
43 [("link.o"
44 ,"-I " ++ mudir ++ "/include -I "
45 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
47 cclib = "-lGL -lX11 -lmupdf -lz -lfreetype -ljpeg\
48 \ -ljbig2dec -lopenjpeg -lmujs\
49 \ -lpthread -L" ++ mudir ++ "/build/native -lcrypto"
51 getincludes :: [String] -> [String]
52 getincludes [] = []
53 getincludes ("-I":arg:tl) = arg : getincludes tl
54 getincludes (_:tl) = getincludes tl
56 isabsinc :: String -> Bool
57 isabsinc [] = False
58 isabsinc (hd:_) = hd == '+' || hd == '/'
60 fixincludes [] = []
61 fixincludes ("-I":d:tl)
62 | isabsinc d = "-I":d:fixincludes tl
63 | otherwise = "-I":inOutDir d:fixincludes tl
64 fixincludes (e:tl) = e:fixincludes tl
66 ocamlKey key | "lablGL/" `isPrefixOf` key = (ocamlc, "-I lablGL", [])
67 | otherwise = case lookup key ocamlflagstbl of
68 Nothing -> (ocamlc, ocamlflags, [])
69 Just (f, []) -> (ocamlc, ocamlflags ++ " " ++ f, [])
70 Just (f, pp) -> (ocamlc, ocamlflags ++ " " ++ f, ["-pp", pp])
72 ocamlKeyN key | "lablGL/" `isPrefixOf` key = (ocamlopt, "-I lablGL", [])
73 | otherwise = case lookup key ocamlflagstbln of
74 Nothing -> (ocamlopt, ocamlflags, [])
75 Just (f, []) -> (ocamlopt, ocamlflags ++ " " ++ f, [])
76 Just (f, pp) -> (ocamlopt, ocamlflags ++ " " ++ f, ["-pp", pp])
78 cKey key | "lablGL/" `isPrefixOf` key = "-Wno-pointer-sign -O2"
79 | otherwise = case lookup key cflagstbl of
80 Nothing -> cflags
81 Just f -> f ++ " " ++ cflags
83 fixppfile s ("File":_:tl) = ("File \"" ++ s ++ "\","):tl
84 fixppfile _ l = l
86 fixpp :: String -> String -> String
87 fixpp r s = unlines [unwords $ fixppfile r $ words x | x <- lines s]
89 ppppe ExitSuccess _ _ = return ()
90 ppppe _ src emsg = error $ fixpp src emsg
92 needsrc key suff = do
93 let src' = key -<.> suff
94 let src = if src' == "help.ml" then inOutDir src' else src'
95 need [src]
96 return src
98 depscaml flags ppflags src = do
99 (Stdout stdout, Stderr emsg, Exit ex) <-
100 cmd ocamldep "-one-line" incs "-I" outdir ppflags src
101 ppppe ex src emsg
102 return stdout
103 where flagl = words flags
104 incs = unwords ["-I " ++ d | d <- getincludes flagl, not $ isabsinc d]
106 compilecaml comp flagl ppflags out src = do
107 let fixedflags = fixincludes flagl
108 (Stderr emsg, Exit ex) <-
109 cmd comp "-c -I" outdir fixedflags "-o" out ppflags src
110 ppppe ex src emsg
111 return ()
113 cmio target suffix oracle ordoracle = do
114 target %> \out -> do
115 let key = dropDirectory1 out
116 src <- needsrc key suffix
117 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
118 let flagl = words flags
119 let dep = out ++ "_dep"
120 need [dep]
121 ddep <- liftIO $ readFile dep
122 let deps = deplist $ parseMakefile ddep
123 need deps
124 compilecaml comp flagl ppflags out src
125 target ++ "_dep" %> \out -> do
126 let key' = dropDirectory1 out
127 let key = reverse (drop 4 $ reverse key')
128 src <- needsrc key suffix
129 (_, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
130 mkfiledeps <- depscaml flags ppflags src
131 writeFileChanged out mkfiledeps
132 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
133 where
134 deps = deplist $ parseMakefile mkfiledeps
135 fit dep = ext == ".cmi" && base /= baseout
136 where (base, ext) = splitExtension dep
137 baseout = dropExtension out
138 need $ map (++ "_dep") depo
139 let ord = reverse . drop 4 $ reverse out
140 unit $ ordoracle $ OcamlOrdOracle ord
141 return ()
142 where
143 deplist [] = []
144 deplist ((_, reqs) : _) =
145 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
147 cmx oracle ordoracle =
148 "//*.cmx" %> \out -> do
149 let key = dropDirectory1 out
150 src <- needsrc key ".ml"
151 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracleN key
152 let flagl = words flags
153 mkfiledeps <- depscaml flags ppflags src
154 need $ deplist $ parseMakefile mkfiledeps
155 unit $ ordoracle $ OcamlOrdOracleN out
156 compilecaml comp flagl ppflags out src
157 where
158 deplist (_ : (_, reqs) : _) =
159 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
160 deplist _ = []
162 main = do
163 depl <- newMVar ([] :: [String])
164 depln <- newMVar ([] :: [String])
165 shakeArgs shakeOptions { shakeFiles = outdir
166 , shakeVerbosity = Normal
167 , shakeChange = ChangeModtimeAndDigest } $ do
168 want [inOutDir "llpp"]
170 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
171 Stdout out <- cmd "git describe --tags --dirty"
172 return (out :: String)
174 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
175 return $ ocamlKey s
177 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
178 return $ ocamlKeyN s
180 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
181 unless (takeExtension s == ".cmi") $
182 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
184 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
185 unless (takeExtension s == ".cmi") $
186 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
188 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey s
190 inOutDir "help.ml" %> \out -> do
191 version <- gitDescribeOracle $ GitDescribeOracle ()
192 need ["mkhelp.sh", "KEYS"]
193 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
194 writeFileChanged out f
196 "//*.o" %> \out -> do
197 let key = dropDirectory1 out
198 flags <- cOracle $ CCmdLineOracle key
199 let src = key -<.> ".c"
200 let dep = out -<.> ".d"
201 unit $ cmd ocamlc "-ccopt"
202 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
203 needMakefileDependencies dep
205 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
206 inOutDir "llpp" %> \out -> do
207 need (globjs ++ map inOutDir ["link.o", "main.cmo", "help.cmo"])
208 cmos <- liftIO $ readMVar depl
209 need cmos
210 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
211 "unix.cma str.cma" (reverse cmos)
212 (inOutDir "link.o") "-cclib" (cclib : globjs)
214 inOutDir "llpp.native" %> \out -> do
215 need (globjs ++ map inOutDir ["link.o", "main.cmx", "help.cmx"])
216 cmxs <- liftIO $ readMVar depln
217 need cmxs
218 unit $ cmd ocamlopt "-g -I lablGL -o" out
219 "unix.cmxa str.cmxa" (reverse cmxs)
220 (inOutDir "link.o") "-cclib" (cclib : globjs)
222 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
223 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
224 cmx ocamlOracleN ocamlOrdOracleN