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