build.sh: respect $CFLAGS
[llpp.git] / Build.hs
blob1059d98e27ab95826167c98661420ab001b91c6f
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
3 import Data.List.Extra
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
28 egl = False
30 ocamlc = "ocamlc.opt"
31 ocamlopt = "ocamlopt.opt"
32 ocamldep = "ocamldep.opt"
33 ocamlflags = "-warn-error +a -w +a -g -safe-string"
34 ocamlflagstbl = [("main.cmo", ("-I lablGL", "sed -f pp.sed"))
35 ,("config.cmo", ("-I lablGL", ""))
37 ocamlflagstbln = [("main.cmx", ("-I lablGL", "sed -f pp.sed"))
38 ,("config.cmx", ("-I lablGL", ""))
40 cflags = "-Wall -Werror -D_GNU_SOURCE -O\
41 \ -g -std=c99 -pedantic-errors\
42 \ -Wunused-parameter -Wsign-compare -Wshadow\
43 \ -DVISAVIS"
44 ++ (if egl then " -DUSE_EGL" else "")
45 cflagstbl =
46 [("link.o"
47 ,"-I " ++ mudir ++ "/include -I "
48 ++ mudir ++ "/thirdparty/freetype/include -Wextra")
50 cclib = "-lGL -lX11 -lmupdf -lz -lfreetype -ljpeg\
51 \ -ljbig2dec -lopenjpeg -lmujs\
52 \ -lpthread -L" ++ mudir ++ "/build/native -lcrypto"
53 ++ (if egl then " -lEGL" else "")
55 getincludes :: [String] -> [String]
56 getincludes [] = []
57 getincludes ("-I":arg:tl) = arg : getincludes tl
58 getincludes (_:tl) = getincludes tl
60 isabsinc :: String -> Bool
61 isabsinc [] = False
62 isabsinc (hd:_) = hd == '+' || hd == '/'
64 fixincludes [] = []
65 fixincludes ("-I":d:tl)
66 | isabsinc d = "-I":d:fixincludes tl
67 | otherwise = "-I":inOutDir d:fixincludes tl
68 fixincludes (e:tl) = e:fixincludes tl
70 ocamlKey comp tbl key
71 | "lablGL/" `isPrefixOf` key = (comp, "-I lablGL", [])
72 | otherwise = case lookup key tbl of
73 Nothing -> (comp, ocamlflags, [])
74 Just (f, []) -> (comp, ocamlflags ++ " " ++ f, [])
75 Just (f, pp) -> (comp, ocamlflags ++ " " ++ f, ["-pp", pp])
77 cKey key | "lablGL/" `isPrefixOf` key = "-Wno-pointer-sign -O2"
78 | otherwise = case lookup key cflagstbl of
79 Nothing -> cflags
80 Just f -> f ++ " " ++ cflags
82 fixppfile s ("File":_:tl) = ("File \"" ++ s ++ "\","):tl
83 fixppfile _ l = l
85 fixpp :: String -> String -> String
86 fixpp r s = unlines [unwords $ fixppfile r $ words x | x <- lines s]
88 ppppe ExitSuccess _ _ = return ()
89 ppppe _ src emsg = error $ fixpp src emsg
91 needsrc key suff = do
92 let src' = key -<.> suff
93 let src = if src' == "help.ml" then inOutDir src' else src'
94 need [src]
95 return src
97 depscaml flags ppflags src = do
98 (Stdout stdout, Stderr emsg, Exit ex) <-
99 cmd ocamldep "-one-line" incs "-I" outdir ppflags src
100 ppppe ex src emsg
101 return stdout
102 where flagl = words flags
103 incs = unwords ["-I " ++ d | d <- getincludes flagl, not $ isabsinc d]
105 compilecaml comp flagl ppflags out src = do
106 let fixedflags = fixincludes flagl
107 (Stderr emsg, Exit ex) <-
108 cmd comp "-c -I" outdir fixedflags "-o" out ppflags src
109 ppppe ex src emsg
110 return ()
112 cmio target suffix oracle ordoracle = do
113 target %> \out -> do
114 let key = dropDirectory1 out
115 src <- needsrc key suffix
116 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
117 let flagl = words flags
118 let dep = out ++ "_dep"
119 need [dep]
120 ddep <- liftIO $ readFile dep
121 let deps = deplist $ parseMakefile ddep
122 need deps
123 compilecaml comp flagl ppflags out src
124 target ++ "_dep" %> \out -> do
125 let ord = dropEnd 4 out
126 let key = dropDirectory1 ord
127 src <- needsrc key suffix
128 (_, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
129 mkfiledeps <- depscaml flags ppflags src
130 writeFileChanged out mkfiledeps
131 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
132 where
133 deps = deplist $ parseMakefile mkfiledeps
134 fit dep = ext == ".cmi" && base /= baseout
135 where (base, ext) = splitExtension dep
136 baseout = dropExtension out
137 need $ map (++ "_dep") depo
138 unit $ ordoracle $ OcamlOrdOracle ord
139 where
140 deplist [] = []
141 deplist ((_, reqs) : _) =
142 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
144 cmx oracle ordoracle =
145 "//*.cmx" %> \out -> do
146 let key = dropDirectory1 out
147 src <- needsrc key ".ml"
148 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracleN key
149 let flagl = words flags
150 mkfiledeps <- depscaml flags ppflags src
151 need $ deplist $ parseMakefile mkfiledeps
152 unit $ ordoracle $ OcamlOrdOracleN out
153 compilecaml comp flagl ppflags out src
154 where
155 deplist (_ : (_, reqs) : _) =
156 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
157 deplist _ = []
159 main = do
160 depl <- newMVar ([] :: [String])
161 depln <- newMVar ([] :: [String])
162 shakeArgs shakeOptions { shakeFiles = outdir
163 , shakeVerbosity = Normal
164 , shakeChange = ChangeModtimeAndDigest } $ do
165 want [inOutDir "llpp"]
167 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
168 Stdout out <- cmd "git describe --tags --dirty"
169 return (out :: String)
171 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
172 return $ ocamlKey ocamlc ocamlflagstbl s
174 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
175 return $ ocamlKey ocamlopt ocamlflagstbln s
177 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
178 unless (takeExtension s == ".cmi") $
179 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
181 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
182 unless (takeExtension s == ".cmi") $
183 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
185 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey s
187 inOutDir "help.ml" %> \out -> do
188 version <- gitDescribeOracle $ GitDescribeOracle ()
189 need ["mkhelp.sh", "KEYS"]
190 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
191 writeFileChanged out f
193 "//*.o" %> \out -> do
194 let key = dropDirectory1 out
195 flags <- cOracle $ CCmdLineOracle key
196 let src = key -<.> ".c"
197 let dep = out -<.> ".d"
198 unit $ cmd ocamlc "-ccopt"
199 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
200 needMakefileDependencies dep
202 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
203 inOutDir "llpp" %> \out -> do
204 need (globjs ++ map inOutDir ["link.o", "main.cmo", "help.cmo"])
205 cmos <- liftIO $ readMVar depl
206 need cmos
207 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
208 "unix.cma str.cma" (reverse cmos)
209 (inOutDir "link.o") "-cclib" (cclib : globjs)
211 inOutDir "llpp.native" %> \out -> do
212 need (globjs ++ map inOutDir ["link.o", "main.cmx", "help.cmx"])
213 cmxs <- liftIO $ readMVar depln
214 need cmxs
215 unit $ cmd ocamlopt "-g -I lablGL -o" out
216 "unix.cmxa str.cmxa" (reverse cmxs)
217 (inOutDir "link.o") "-cclib" (cclib : globjs)
219 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
220 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
221 cmx ocamlOracleN ocamlOrdOracleN