calcactive does not make sense for history
[llpp.git] / Build.hs
blob98947004a81245d95b1ce9907d8f9dc83b718879
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
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 comp tbl key
67 | "lablGL/" `isPrefixOf` key = (comp, "-I lablGL", [])
68 | otherwise = case lookup key tbl of
69 Nothing -> (comp, ocamlflags, [])
70 Just (f, []) -> (comp, ocamlflags ++ " " ++ f, [])
71 Just (f, pp) -> (comp, ocamlflags ++ " " ++ f, ["-pp", pp])
73 cKey key | "lablGL/" `isPrefixOf` key = "-Wno-pointer-sign -O2"
74 | otherwise = case lookup key cflagstbl of
75 Nothing -> cflags
76 Just f -> f ++ " " ++ cflags
78 fixppfile s ("File":_:tl) = ("File \"" ++ s ++ "\","):tl
79 fixppfile _ l = l
81 fixpp :: String -> String -> String
82 fixpp r s = unlines [unwords $ fixppfile r $ words x | x <- lines s]
84 ppppe ExitSuccess _ _ = return ()
85 ppppe _ src emsg = error $ fixpp src emsg
87 needsrc key suff = do
88 let src' = key -<.> suff
89 let src = if src' == "help.ml" then inOutDir src' else src'
90 need [src]
91 return src
93 depscaml flags ppflags src = do
94 (Stdout stdout, Stderr emsg, Exit ex) <-
95 cmd ocamldep "-one-line" incs "-I" outdir ppflags src
96 ppppe ex src emsg
97 return stdout
98 where flagl = words flags
99 incs = unwords ["-I " ++ d | d <- getincludes flagl, not $ isabsinc d]
101 compilecaml comp flagl ppflags out src = do
102 let fixedflags = fixincludes flagl
103 (Stderr emsg, Exit ex) <-
104 cmd comp "-c -I" outdir fixedflags "-o" out ppflags src
105 ppppe ex src emsg
106 return ()
108 cmio target suffix oracle ordoracle = do
109 target %> \out -> do
110 let key = dropDirectory1 out
111 src <- needsrc key suffix
112 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
113 let flagl = words flags
114 let dep = out ++ "_dep"
115 need [dep]
116 ddep <- liftIO $ readFile dep
117 let deps = deplist $ parseMakefile ddep
118 need deps
119 compilecaml comp flagl ppflags out src
120 target ++ "_dep" %> \out -> do
121 let ord = dropEnd 4 out
122 let key = dropDirectory1 ord
123 src <- needsrc key suffix
124 (_, flags, ppflags) <- oracle $ OcamlCmdLineOracle key
125 mkfiledeps <- depscaml flags ppflags src
126 writeFileChanged out mkfiledeps
127 let depo = deps ++ [dep -<.> ".cmo" | dep <- deps, fit dep]
128 where
129 deps = deplist $ parseMakefile mkfiledeps
130 fit dep = ext == ".cmi" && base /= baseout
131 where (base, ext) = splitExtension dep
132 baseout = dropExtension out
133 need $ map (++ "_dep") depo
134 unit $ ordoracle $ OcamlOrdOracle ord
135 where
136 deplist [] = []
137 deplist ((_, reqs) : _) =
138 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
140 cmx oracle ordoracle =
141 "//*.cmx" %> \out -> do
142 let key = dropDirectory1 out
143 src <- needsrc key ".ml"
144 (comp, flags, ppflags) <- oracle $ OcamlCmdLineOracleN key
145 let flagl = words flags
146 mkfiledeps <- depscaml flags ppflags src
147 need $ deplist $ parseMakefile mkfiledeps
148 unit $ ordoracle $ OcamlOrdOracleN out
149 compilecaml comp flagl ppflags out src
150 where
151 deplist (_ : (_, reqs) : _) =
152 [if takeDirectory1 n == outdir then n else inOutDir n | n <- reqs]
153 deplist _ = []
155 main = do
156 depl <- newMVar ([] :: [String])
157 depln <- newMVar ([] :: [String])
158 shakeArgs shakeOptions { shakeFiles = outdir
159 , shakeVerbosity = Normal
160 , shakeChange = ChangeModtimeAndDigest } $ do
161 want [inOutDir "llpp"]
163 gitDescribeOracle <- addOracle $ \(GitDescribeOracle ()) -> do
164 Stdout out <- cmd "git describe --tags --dirty"
165 return (out :: String)
167 ocamlOracle <- addOracle $ \(OcamlCmdLineOracle s) ->
168 return $ ocamlKey ocamlc ocamlflagstbl s
170 ocamlOracleN <- addOracle $ \(OcamlCmdLineOracleN s) ->
171 return $ ocamlKey ocamlopt ocamlflagstbln s
173 ocamlOrdOracle <- addOracle $ \(OcamlOrdOracle s) ->
174 unless (takeExtension s == ".cmi") $
175 liftIO $ modifyMVar_ depl $ \l -> return $ s:l
177 ocamlOrdOracleN <- addOracle $ \(OcamlOrdOracleN s) ->
178 unless (takeExtension s == ".cmi") $
179 liftIO $ modifyMVar_ depln $ \l -> return $ s:l
181 cOracle <- addOracle $ \(CCmdLineOracle s) -> return $ cKey s
183 inOutDir "help.ml" %> \out -> do
184 version <- gitDescribeOracle $ GitDescribeOracle ()
185 need ["mkhelp.sh", "KEYS"]
186 Stdout f <- cmd "/bin/sh mkhelp.sh KEYS" version
187 writeFileChanged out f
189 "//*.o" %> \out -> do
190 let key = dropDirectory1 out
191 flags <- cOracle $ CCmdLineOracle key
192 let src = key -<.> ".c"
193 let dep = out -<.> ".d"
194 unit $ cmd ocamlc "-ccopt"
195 [flags ++ " -MMD -MF " ++ dep ++ " -o " ++ out] "-c" src
196 needMakefileDependencies dep
198 let globjs = map (inOutDir . (++) "lablGL/ml_") ["gl.o", "glarray.o", "raw.o"]
199 inOutDir "llpp" %> \out -> do
200 need (globjs ++ map inOutDir ["link.o", "main.cmo", "help.cmo"])
201 cmos <- liftIO $ readMVar depl
202 need cmos
203 unit $ cmd ocamlc "-g -custom -I lablGL -o" out
204 "unix.cma str.cma" (reverse cmos)
205 (inOutDir "link.o") "-cclib" (cclib : globjs)
207 inOutDir "llpp.native" %> \out -> do
208 need (globjs ++ map inOutDir ["link.o", "main.cmx", "help.cmx"])
209 cmxs <- liftIO $ readMVar depln
210 need cmxs
211 unit $ cmd ocamlopt "-g -I lablGL -o" out
212 "unix.cmxa str.cmxa" (reverse cmxs)
213 (inOutDir "link.o") "-cclib" (cclib : globjs)
215 cmio "//*.cmi" ".mli" ocamlOracle ocamlOrdOracle
216 cmio "//*.cmo" ".ml" ocamlOracle ocamlOrdOracle
217 cmx ocamlOracleN ocamlOrdOracleN